home *** CD-ROM | disk | FTP | other *** search
- diff -c -r +new-file pl/STAMP pl/STAMP
- *** pl/STAMP Wed Mar 2 18:10:32 1994
- --- pl/STAMP Tue Mar 22 12:05:08 1994
- ***************
- *** 1 ****
- ! Wed Mar 2 18:08:00 MET 1994
- --- 1 ----
- ! Tue Mar 22 12:03:06 MET 1994
- diff -c -r +new-file pl/VERSION pl/VERSION
- *** pl/VERSION Wed Mar 2 15:32:01 1994
- --- pl/VERSION Mon Mar 21 17:45:45 1994
- ***************
- *** 1 ****
- ! 1.8.9
- --- 1 ----
- ! 1.8.10
- diff -c -r +new-file pl/library/quintus.pl pl/library/quintus.pl
- *** pl/library/quintus.pl Wed Mar 2 15:32:30 1994
- --- pl/library/quintus.pl Mon Mar 21 17:46:13 1994
- ***************
- *** 1,4 ****
- ! /* quintus.pl,v 1.7 1994/03/02 14:32:30 jan Exp
-
- Copyright (c) 1990 Jan Wielemaker. All rights reserved.
- jan@swi.psy.uva.nl
- --- 1,4 ----
- ! /* quintus.pl,v 1.8 1994/03/21 16:46:13 jan Exp
-
- Copyright (c) 1990 Jan Wielemaker. All rights reserved.
- jan@swi.psy.uva.nl
- ***************
- *** 28,34 ****
- --- 28,36 ----
- , otherwise/0
- , (initialization)/1
- , absolute_file_name/3
- + , prolog_load_context/2
- , numbervars/3
- + , statistics/2
- ]).
-
- /********************************
- ***************
- *** 79,84 ****
- --- 81,108 ----
- concat(Base, Ext, Name).
-
-
- + % prolog_load_context(+Key, -Value)
- + %
- + % Provides context information for term_expansion and directives.
- + % Note that only the line-number info is valid for the
- + % '$stream_position'
- +
- + :- module_transparent
- + prolog_load_context/2.
- +
- + prolog_load_context(module, M) :-
- + context_module(M).
- + prolog_load_context(file, F) :-
- + source_location(F, _).
- + prolog_load_context(stream, S) :-
- + current_input(S).
- + prolog_load_context(directory, D) :-
- + source_location(F, _),
- + '$file_dir_name'(F, D).
- + prolog_load_context(term_position, '$stream_position'(0,L,0,0,0)) :-
- + source_location(_, L).
- +
- +
- /********************************
- * META PREDICATES *
- *********************************/
- ***************
- *** 141,146 ****
- --- 165,198 ----
-
- random(Min, Max, Value) :-
- Value is Min + random(Max).
- +
- + /*******************************
- + * STATISTICS *
- + *******************************/
- +
- + :- recorda('$runtime', 0, _).
- +
- + statistics(runtime, [Total, New]) :- !,
- + system:statistics(cputime, Time),
- + Total is integer(Time * 1000),
- + recorded('$runtime', Old, Ref),
- + New is Total - Old,
- + erase(Ref),
- + recorda('$runtime', Total, _).
- + statistics(program, [InUse, _Free]) :- !,
- + system:statistics(heapused, InUse).
- + statistics(heap, Stat) :- !,
- + statistics(program, Stat).
- + statistics(global_stack, [InUse, Free]) :- !,
- + system:statistics(globalused, InUse),
- + system:statistics(globallimit, Limit),
- + Free is Limit - InUse.
- + statistics(local_stack, [InUse, Free]) :- !,
- + system:statistics(localused, InUse),
- + system:statistics(locallimit, Limit),
- + Free is Limit - InUse.
- + statistics(trail, [InUse]) :- !,
- + system:statistics(trailused, InUse).
-
-
- /********************************
- diff -c -r +new-file pl/src/md-hp.h pl/src/md-hp.h
- *** pl/src/md-hp.h Mon Dec 6 18:00:51 1993
- --- pl/src/md-hp.h Mon Mar 21 17:46:38 1994
- ***************
- *** 1,4 ****
- ! /* md-hp.h,v 1.18 1993/12/06 17:00:51 jan Exp
-
- Copyright (c) 1990 Jan Wielemaker. All rights reserved.
- See ../LICENCE to find out about your rights.
- --- 1,4 ----
- ! /* md-hp.h,v 1.19 1994/03/21 16:46:38 jan Exp
-
- Copyright (c) 1990 Jan Wielemaker. All rights reserved.
- See ../LICENCE to find out about your rights.
- ***************
- *** 43,48 ****
- --- 43,51 ----
- library function vsprintf().
- He successfully compiled on a hp9000s700 running hpux 8.07.
- The resulting binary runs on both machines.
- +
- + Version 1.8.10 includes some patches by Dave Sherratt for the HP cc
- + compiler.
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
-
- #define MACHINE "hp"
- ***************
- *** 61,67 ****
- #define M_CFLAGS
- #else /* Use HP-UX cc */
- #define M_CC cc
- ! #define M_OPTIMIZE +O1 +Obb650 /* In HP-UX 8.07, can use +O3 */
- #define M_LDFLAGS -O -Wl,-a archive
- #define M_CFLAGS -Aa -D_HPUX_SOURCE -Dunix -Dhpux -I/usr/local/include -I/usr/local/include/readline
- #endif
- --- 64,70 ----
- #define M_CFLAGS
- #else /* Use HP-UX cc */
- #define M_CC cc
- ! #define M_OPTIMIZE +O1 +Obb700 /* In HP-UX 8.07, can use +O3 */
- #define M_LDFLAGS -O -Wl,-a archive
- #define M_CFLAGS -Aa -D_HPUX_SOURCE -Dunix -Dhpux -I/usr/local/include -I/usr/local/include/readline
- #endif
- diff -c -r +new-file pl/src/md-linux.h pl/src/md-linux.h
- *** pl/src/md-linux.h Wed Mar 2 15:32:50 1994
- --- pl/src/md-linux.h Mon Mar 21 17:46:40 1994
- ***************
- *** 1,4 ****
- ! /* md-linux.h,v 1.19 1994/03/02 14:32:50 jan Exp
-
- Copyright (c) 1992 Jan Wielemaker/Pieter Olivier. All rights reserved.
- See ../LICENCE to find out about your rights.
- --- 1,4 ----
- ! /* md-linux.h,v 1.20 1994/03/21 16:46:40 jan Exp
-
- Copyright (c) 1992 Jan Wielemaker/Pieter Olivier. All rights reserved.
- See ../LICENCE to find out about your rights.
- ***************
- *** 33,38 ****
- --- 33,46 ----
- results in multiple symbol declaration when SWI-Prolog is linked.
- As a temporary fix remove /usr/lib/libtermcap.sa while linking
- SWI-Prolog.
- +
- + Thu Mar 10 22:14:20 1994
- + Updated version 1.8.9. The stdio file structure elements were
- + changed with libc 4.5.8 and above. The linux stdio now uses the
- + libio structures. The old (and new) versions still don't work
- + the way RESET_STDIN is meant to work. There seems to be no portable
- + way to handle flushing all to-be-input characters when doing a save/1.
- + Kayvan Sylvan (kayvan@Sylvan.COM) also (kayvan@Quintus.COM).
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
-
- #define M_CC gcc
- ***************
- *** 39,45 ****
- #define M_OPTIMIZE -O2
- /*#define M_OPTIMIZE -g*/
- #define M_LDFLAGS -static
- ! #define M_CFLAGS -ansi -pedantic -Wall -funsigned-char
- #define M_LIBS -lm -ltermcap -lreadline
-
- /* compiler */
- --- 47,54 ----
- #define M_OPTIMIZE -O2
- /*#define M_OPTIMIZE -g*/
- #define M_LDFLAGS -static
- ! /*#define M_CFLAGS -ansi -pedantic -Wall -funsigned-char*/
- ! #define M_CFLAGS -Wall -funsigned-char
- #define M_LIBS -lm -ltermcap -lreadline
-
- /* compiler */
- ***************
- *** 73,78 ****
- --- 82,93 ----
- #define DIR_INCLUDE2 <dirent.h>
- #define TERMIO_INCLUDE <termio.h>
- #define O_GETCWD 1
- +
- + /* This is for the newer libc (4.5.8+) */
- + #ifdef _STDIO_USES_IOSTREAM
- + #define _gptr _IO_read_ptr
- + #define _egptr _IO_read_end
- + #endif
-
- #include <linux/limits.h>
-
- diff -c -r +new-file pl/src/md-sgi.h pl/src/md-sgi.h
- *** pl/src/md-sgi.h Wed Mar 2 15:32:52 1994
- --- pl/src/md-sgi.h Mon Mar 21 17:46:41 1994
- ***************
- *** 1,4 ****
- ! /* md-sgi.h,v 1.6 1994/03/02 14:32:52 jan Exp
-
- Copyright (c) 1990 Jan Wielemaker. All rights reserved.
- See ../LICENCE to find out about your rights.
- --- 1,4 ----
- ! /* md-sgi.h,v 1.7 1994/03/21 16:46:41 jan Exp
-
- Copyright (c) 1990 Jan Wielemaker. All rights reserved.
- See ../LICENCE to find out about your rights.
- ***************
- *** 13,24 ****
- It appears `O_FOREIGN 1' gives problems on some SGI archiectures. It you
- are not a C-hacker change this into O_FOREIGN 0. Otherwise you might
- want to start debugging.
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
-
- #define M_CC gcc
- #define M_OPTIMIZE -O2
- #define M_LDFLAGS
- ! #define M_CFLAGS
- #define M_LIBS -lm -ltermcap
-
-
- --- 13,26 ----
- It appears `O_FOREIGN 1' gives problems on some SGI archiectures. It you
- are not a C-hacker change this into O_FOREIGN 0. Otherwise you might
- want to start debugging.
- +
- + Added -DANSI -D_BSD_SIGNALS after report from Fergus Henderson
- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
-
- #define M_CC gcc
- #define M_OPTIMIZE -O2
- #define M_LDFLAGS
- ! #define M_CFLAGS -DANSI -D_BSD_SIGNALS
- #define M_LIBS -lm -ltermcap
-
-
- diff -c -r +new-file pl/src/pl-alloc.c pl/src/pl-alloc.c
- *** pl/src/pl-alloc.c Wed Mar 2 15:32:54 1994
- --- pl/src/pl-alloc.c Mon Mar 21 17:46:42 1994
- ***************
- *** 1,4 ****
- ! /* pl-alloc.c,v 1.12 1994/03/02 14:32:54 jan Exp
-
- Copyright (c) 1990 Jan Wielemaker. All rights reserved.
- See ../LICENCE to find out about your rights.
- --- 1,4 ----
- ! /* pl-alloc.c,v 1.13 1994/03/21 16:46:42 jan Exp
-
- Copyright (c) 1990 Jan Wielemaker. All rights reserved.
- See ../LICENCE to find out about your rights.
- ***************
- *** 93,99 ****
-
- n = ALLOCROUND(n);
- statistics.heap -= n;
- ! DEBUG(9, printf("freed %ld bytes at %ld\n", n, (unsigned long)p));
-
- if (n <= ALLOCFAST)
- { n /= sizeof(align_type);
- --- 93,100 ----
-
- n = ALLOCROUND(n);
- statistics.heap -= n;
- ! DEBUG(9, printf("freed %ld bytes at %ld\n",
- ! (unsigned long)n, (unsigned long)p));
-
- if (n <= ALLOCFAST)
- { n /= sizeof(align_type);
- diff -c -r +new-file pl/src/pl-file.c pl/src/pl-file.c
- *** pl/src/pl-file.c Wed Mar 2 15:33:04 1994
- --- pl/src/pl-file.c Mon Mar 21 17:46:43 1994
- ***************
- *** 1,4 ****
- ! /* pl-file.c,v 1.20 1994/03/02 14:33:04 jan Exp
-
- Copyright (c) 1990 Jan Wielemaker. All rights reserved.
- See ../LICENCE to find out about your rights.
- --- 1,4 ----
- ! /* pl-file.c,v 1.21 1994/03/21 16:46:43 jan Exp
-
- Copyright (c) 1990 Jan Wielemaker. All rights reserved.
- See ../LICENCE to find out about your rights.
- ***************
- *** 760,766 ****
- --- 760,770 ----
- struct timeval t, *to;
- real time;
- int n, max = 0;
- + #if hpux
- + extern int select(size_t, int *, int *, int *, const struct timeval *);
- + #else
- extern int select(int, fd_set *, fd_set *, fd_set *, struct timeval *);
- + #endif
-
- FD_ZERO(&fds);
- while( isList(*streams) )
- diff -c -r +new-file pl/src/pl-itf.h pl/src/pl-itf.h
- *** pl/src/pl-itf.h Wed Mar 2 15:33:12 1994
- --- pl/src/pl-itf.h Mon Mar 21 17:46:44 1994
- ***************
- *** 1,4 ****
- ! /* pl-itf.h,v 1.40 1994/03/02 14:33:12 jan Exp
-
- Copyright (c) 1990 Jan Wielemaker. All rights reserved.
- See ../LICENCE to find out about your rights.
- --- 1,4 ----
- ! /* pl-itf.h,v 1.41 1994/03/21 16:46:44 jan Exp
-
- Copyright (c) 1990 Jan Wielemaker. All rights reserved.
- See ../LICENCE to find out about your rights.
- ***************
- *** 11,17 ****
- #define PL_INCLUDED
-
- #ifndef PLVERSION
- ! #define PLVERSION "1.8.9 March 1994"
- #endif
-
- #if __GNUC__ && !__STRICT_ANSI__
- --- 11,17 ----
- #define PL_INCLUDED
-
- #ifndef PLVERSION
- ! #define PLVERSION "1.8.10 March 1994"
- #endif
-
- #if __GNUC__ && !__STRICT_ANSI__
- diff -c -r +new-file pl/src/pl-os.c pl/src/pl-os.c
- *** pl/src/pl-os.c Wed Mar 2 17:50:44 1994
- --- pl/src/pl-os.c Mon Mar 21 17:49:36 1994
- ***************
- *** 1,4 ****
- ! /* pl-os.c,v 1.42 1994/03/02 16:50:44 jan Exp
-
- Copyright (c) 1990 Jan Wielemaker. All rights reserved.
- See ../LICENCE to find out about your rights.
- --- 1,4 ----
- ! /* pl-os.c,v 1.44 1994/03/21 16:49:36 jan Exp
-
- Copyright (c) 1990 Jan Wielemaker. All rights reserved.
- See ../LICENCE to find out about your rights.
- ***************
- *** 16,21 ****
- --- 16,24 ----
- #if OS2 && EMX
- #include <os2.h> /* this has to appear before pl-incl.h */
- #endif
- + #ifdef linux
- + #include <stdio.h>
- + #endif
- #include "pl-incl.h"
- #include "pl-ctype.h"
- #include "pl-itf.h"
- ***************
- *** 1385,1391 ****
- }
-
- strcpy(path, CWDdir);
- ! strcpy(&path[CWDlen], file);
- if ( strchr(file, '.') || strchr(file, '/') )
- return canonisePath(path);
- else
- --- 1388,1395 ----
- }
-
- strcpy(path, CWDdir);
- ! if ( file[0] != EOS )
- ! strcpy(&path[CWDlen], file);
- if ( strchr(file, '.') || strchr(file, '/') )
- return canonisePath(path);
- else
- ***************
- *** 1617,1622 ****
- --- 1621,1643 ----
-
- #define savestring(x) strcpy(xmalloc(1 + strlen(x)), (x))
-
- + static Char
- + GetRawChar(void)
- + { unsigned char chr;
- +
- + if ( PL_dispatch_events )
- + { while((*PL_dispatch_events)() != PL_DISPATCH_INPUT)
- + ;
- + }
- +
- + if (read(0, &chr, 1) == 0)
- + return EOF;
- + else
- + return chr;
- + }
- +
- +
- +
- Char
- GetChar(void)
- { static char *line; /* read line */
- ***************
- *** 1626,1648 ****
- Char c;
-
- if ( ttymode == TTY_RAW )
- ! { if ( PL_dispatch_events )
- ! { for(;;)
- ! { if ( (*PL_dispatch_events)() == PL_DISPATCH_INPUT )
- ! { char chr;
- !
- ! if (read(0, &chr, 1) == 0)
- ! c = EOF;
- ! else
- ! c = (Char) chr;
- ! break;
- ! }
- ! }
- ! } else
- ! { char chr; /* don't use getchar(); I/O buffer */
- ! /* might not be empty after save() */
- ! c = (read(0, &chr, 1) == 0 ? EOF : chr);
- }
- } else
- { if ( !line )
- { ttybuf buf;
- --- 1647,1667 ----
- Char c;
-
- if ( ttymode == TTY_RAW )
- ! { c = GetRawChar();
- ! } else if ( status.notty )
- ! { if ( !line )
- ! { extern int Output;
- ! int old = Output;
- ! Output = 1;
- ! Putf("%s", PrologPrompt());
- ! pl_flush();
- ! Output = old;
- !
- ! line = "ok";
- }
- +
- + if ( (c=GetRawChar()) == '\n' )
- + line = NULL;
- } else
- { if ( !line )
- { ttybuf buf;
- ***************
- *** 1682,1687 ****
- --- 1701,1707 ----
-
- source_line_no = sln;
- source_file_name = sfn;
- +
- return c;
- }
-
- diff -c -r +new-file pl/src/pl-read.c pl/src/pl-read.c
- *** pl/src/pl-read.c Wed Mar 2 15:33:23 1994
- --- pl/src/pl-read.c Mon Mar 21 17:46:46 1994
- ***************
- *** 1,4 ****
- ! /* pl-read.c,v 1.15 1994/03/02 14:33:23 jan Exp
-
- Copyright (c) 1990 Jan Wielemaker. All rights reserved.
- See ../LICENCE to find out about your rights.
- --- 1,4 ----
- ! /* pl-read.c,v 1.16 1994/03/21 16:46:46 jan Exp
-
- Copyright (c) 1990 Jan Wielemaker. All rights reserved.
- See ../LICENCE to find out about your rights.
- ***************
- *** 97,103 ****
- char *here; /* current position in read buffer */
- int stream; /* stream we are reading from */
- FILE *fd; /* file descriptor we are reading from */
- - bool doExtend; /* extension mode on? */
- } rb;
-
- #if O_PCE
- --- 97,102 ----
- ***************
- *** 125,131 ****
- rb_stack[read_nesting++] = rb;
- rb = rb_stack[read_nesting];
- #endif /* O_PCE */
- - rb.doExtend = (Input == 0 && status.notty == FALSE);
- rb.stream = Input;
- rb.fd = checkInput(rb.stream);
- source_file_name = currentStreamName();
- --- 124,129 ----
- diff -c -r +new-file pl/src/sun-types.h pl/src/sun-types.h
- *** pl/src/sun-types.h
- --- pl/src/sun-types.h Mon Mar 21 17:46:47 1994
- ***************
- *** 0 ****
- --- 1,43 ----
- + /* sun-types.h,v 1.1 1994/03/21 16:46:47 jan Exp
- +
- + Part of XPCE
- + Designed and implemented by Anjo Anjewierden and Jan Wielemaker
- + E-mail: jan@swi.psy.uva.nl
- +
- + Copyright (C) 1994 University of Amsterdam. All rights reserved.
- + */
- +
- + /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
- + Missing sun type declarations to allow gcc -Wall
- + - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
- +
- + extern int sscanf (const char *, const char *, ...);
- + extern int fscanf (FILE *, const char *, ...);
- + extern int printf (const char *, ...);
- + extern int _filbuf (FILE *);
- + extern int _flsbuf (unsigned int, FILE *);
- + extern long time (long *);
- + extern int gethostname(char *name, int namelen);
- + extern int fprintf (FILE *, const char *, ...);
- + extern int fflush (FILE *);
- + extern long int strtol (const char *, char **, int);
- + extern int vprintf (const char *, char * );
- + extern int vsprintf (char *, const char *, char * );
- + extern int vfprintf (FILE *, const char *, char * );
- + extern long unsigned int fread (void *, long unsigned int,
- + long unsigned int, FILE *);
- + extern long unsigned int fwrite (const void *, long unsigned int,
- + long unsigned int, FILE *);
- + extern int ungetc (int, FILE *);
- + extern int getw(FILE *stream);
- + extern int putw(int data, FILE *stream);
- + extern int pclose(FILE *stream);
- + extern int fclose(FILE *stream);
- + extern void bcopy(void *b1, void *b2, int length);
- + extern int fseek (FILE *, long int, int);
- + extern char *getwd(char *pathname);
- + extern int ioctl(int fd, int request, void *arg);
- + extern void bzero(void *b, int length);
- + extern int brk(void *addr);
- + extern void *sbrk(int incr);
- + extern int system (const char *);
-